; System 7 modifications ; courier 9pt -9 spacing tabs: .875 1.5 3.625 ; need to change modification in vers RSRC ; flush caches in trap; fix d0 saves for flushes ; fixed s,; added ucase in word_ ; Load equates for Toolbox, Quickdraw LIST OFF INCLUDE "library.asm" INCLUDE "equates.asm" INCLUDE "yerk.macro" * gestalt EQU $a1ad newhandc EQU $a322 newPtrc EQU $a31e stripAddress EQU $a055 waitNextEvt EQU $a860 HWPriv EQU $a198 GLOBAL $200,$200 ENDG TFILE "YERK.BIN" RFILE "YERK",APPL,YERK,$2100 ; has bundle,init ; Rsize EQU 400 ; Maximum depth of ret+mstack Rbytes EQU -Rsize*4 ; Number of bytes for ret+mstack MSbytes EQU 1200 ; 300 cells on methods stack sysVects EQU 17 ; how many system vectors + 1 (for len) sysVecSz EQU sysVects*4 ; total len of system vector table ; 'SAVE' HEADER EQUATES. udp EQU 0 ; User dictionary pointer ufence EQU 4 ; User fence pointer uvocl EQU 8 ; User vocabulary pointer ulatest EQU 12 ; Latest NFA. headlen EQU 16 ; Length of header ; Finder Handle Offsets opflag EQU 0 ; Open/Print flag numfiles EQU 2 ; Number of files volrnum EQU 0 ; Volume reference number ftype EQU 2 ; File type fvernum EQU 6 ; File's version number fname EQU 8 ; File name ( ) f.handle EQU 16 ; Offset to finder handle * SEG 1,48 bra.s start installed data /0 ; 0 if cold; 1 if warm; 2 if application getInstL lea installed(PC),a2 ; get Installed address in a2 rts start lea installed(PC),a2 ; see if this is a reboot btst #0,(a2) ; if true, mem already acquired, bne.s already ; skip initialization code sjsr getDict ; load seg & get user dict size in d1 clr.l -(sp) move.l #$434F4445,-(sp) ; CODE move.w #2,-(sp) _getResource move.l (sp),a0 ; keep handle on stack clr.l -(sp) ; set up to get size of seg 2 move.l a0,-(sp) _SizeRsrc move.l (sp)+,d2 ; got size in d2 move.l (sp),a0 ; recover handle _Hunlock btst #1,(a2) ; if true, this is application bne.s isApp ; don't change code size add.l d2,d1 ; add nucleus length isApp move.l d1,d0 _SetHandleSize tst.l d0 ; did we get it? beq.s gotit move.w #3,-(sp) _sysbeep _exitToShell gotit move.l (sp)+,a0 _Hlock lea installed(PC),a0 ori.b #1,(a0) ; set true for installed sjmp origin already sjmp coldvec ENDR * SEG 2,48 ; begin USER initialization data origin bra ftInit ; branch around initialization da one EQU origin segStart EQU origin-4 lkorigin EQU origin ; null link for first entry yerkID ASC "3640" ; Release, version, revision, 0 ADJST initLast DATA Lastdef-origin ; origin + 8: last definition addr initFenc DATA Lastdef-origin ; fence initS0 DATA 0 ; offset from A3 for initial A7 (SP) initR0 DATA 0 ; offset from A3 for initial A6 initmp DATA 0 ; offset from A3 for initial D5 initDP DATA 0 ; DP - starts past sys vector table initVocl DATA 0 ; VOC-LINK - last COLD init Userror DATA 0 ; Error during load memsize DATA 300000 ; user dictionary size for CODE2 memPtr DATA 0 ; abs ptr to the user dict heap userdp DATA 0 ; Pointer to the user dict heap stksize DATA $ffffdcd8 ; 9000 stack size ; ; End USER initialization data ; ftInit link a6,#rbytes ; a6=R0,a7=S0 return stack pea -4(a5) _InitGraf ; initGraf(@thePort) lea origin(PC),a3 ; a3 -> code base at load lea stksize(PC),a0 move.l (a0),d1 lea 0(a7,d1.l),a0 ; leave stack space _setApplLimit _MaxApplZone _maxMem ; force purge of the heap * sjsr getInstL ; see if this is a reboot-from seg0 btst #1,(a2) ; if true, this is a program, so skip next bne.s noload jsr loaduser(PC) ; load application dictionary if any noload moveq #(initS0-origin),d7 ; put offset into D7 move.l SP,d0 ; store SP in d0 sub.l a3,d0 ; reference to yerk base move.l d0,0(a3,d7.l) ; inits0 now has offset to data stk move.l a6,d0 ; A6 points to methods stack sub.l a3,d0 ; reference to yerk base lea initmp(PC),a2 ; Init methods stack for cold load move.l d0,(a2) ; initmp now has mstack offset subi.l #msbytes,d0 ; Leave 300 cells for M stack move.l d0,4(a3,d7.l) ; initr0 now has offset to ret stk * COLDVEC bra.s ECLD ; jump to cold start WARMVEC bra.s EWRM ; jump to warm start ; =======Inner Interpreter =========== donext move.l (a4)+,d6 ; get next threaded instruction (32bit) move.l 0(a3,d6.l),d7 ; get code address jmp 0(a3,d7.l) ; jump to code addr relative to a3 nop ECLD movea.l #applScratch,a2 ; fill scratch with warm start move.w #$4ef9,(a2)+ ; jmp lea ewrm(PC),a0 move.l a0,(a2) * lea cld1(PC),a4 ; A4 is IP in inner interpreter bra.s EWRM1 EWRM lea warm1(PC),a4 ; A4 is IP in inner interpreter EWRM1 lea origin(PC),a3 moveq #(initS0-origin),d7 ; get address of initS0 in D7 movea.l 0(a3,d7.l),SP ; pickup s0 address in SP adda.l a3,SP movea.l 4(a3,d7.l),a6 ; pickup r0 address in a6 adda.l a3,a6 move.l initmp(PC),d5 ; Pick methods stack pointer add.l a3,d5 gonext ; ; GETDICT call from seg 0 getDict lea memsize(PC),a1 move.l (a1),d1 rts ; warm1 cfas cls,abort,semis ; Loaduser routine loads the user dictionary if there is one to be loaded. ; First get some Heap to read the user dictionary into. We want ; get as much heap as there is available, minus some for the system. loaduser lea memsize(PC),a1 ; get initial space move.l (a1),d0 lea nextdef+2(PC),a0 ; get top of nuc abs sub.l a0,d0 ; get user dict memsize acquired add.l a3,d0 ; move.l d0,(a1) asr.l #2,d0 ; number of long words to clear clm clr.l (a0)+ dbra d0,clm lea nextdef+2(PC),a0 lea memptr(PC),a2 move.l a0,(a2) ; Save the memory pointer ; set up DP suba.l a3,a0 ; a0 has relative base of user dict lea initdp(PC),a2 move.l a0,(a2) ; Set default dp andi.l #$FFFFFF,(a2) ; mask out hi byte ????WHY add.l #sysvecSz,(a2) ; bump dp past system vector table * lea userdp(PC),a2 ; Save pointer to dict. begin move.l a0,(a2) andi.l #$FFFFFF,(a2) jsr loadcom(PC) rts ; ; Get the finder handle and see if there is file to be opened ; loadcom movea.l f.handle(a5),a0 ; Get finder handle movea.l (a0),a0 ; Dereference it tst.w (a0) ; Check if open or print beq load010 ; ok to open movea.l #2,a0 ; error. we don't print bra loaderror ; The file is to be opened. See if there are any files to open. load010 tst.w numfiles(a0) ; any files to open? bne load020 ; at least one movea.l #1,a0 ; none. just the nucleus bra loaderror ; We have at least one file to be opened. Even if there are more than ; one at this point we are only going to open the first file picked. load020 adda.l #4,a0 ; a0 points past the header move.l ftype(a0),a1 ; get filetype of the file cmpa.l #$434f4d20,a1 ; is it 'COM ' ? bne loaderror lea usefcb(PC),a1 ; load pointer to usefcb lea fname(a0),a2 ; load pointer to filename move.l a2,IoFileName(a1) ; set file pointer in the fcb lea (a0),a2 ; load pointer to VRefNum move.w (a2),IoVRefNum(a1) ; set VRefNum in the fcb move.b #1,IoPermssn(a1) ; set i/o permission to readonly move.l a1,a0 ; Fcb in a0 for call _open ; Open the file tst.w IoResult(a0) ; Check for errors beq load030 ; continue if ok movea.l IoResult(a0),a0 ; error code bra loaderror ; Off to process errors ; Now get the file size so that we know how much to read in. load030 movea.l a1,a0 ; get the fcb back in a0 _getfileinfo ; get info on the file tst.w IoResult(a0) ; Check for errors beq load040 ; continue if ok movea.l IoResult(a0),a0 ; error code bra loaderror ; Off to process errors load040 lea nextdef+2(PC),a4 ; Get buffer addr move.l IoflLgLen(a0),d1 ; Get the logical length of file movea.l a1,a0 ; Fcb again move.l a4,iobuffer(a0) ; Set buffer pointer for data in move.l #headlen,IoReqCount(a0) ; Number of bytes to read clr.l IoPosMode(a0) ; Read from beginning of file clr.l IoPosOffset(a0) ; offset by 0 _read tst.w IoResult(a0) ; Check for errors beq load060 ; continue if ok movea.l IoResult(a0),a0 ; error code bra.s loaderror ; Off to process errors ; Initialize COLD load variables so that the user dictionary is included ; when the FORTH system is brought up. load060 lea initdp(PC),a2 move.l (a4),(a2) ; Set dictionary pointer lea initfenc(PC),a2 move.l ufence(a4),(a2) ; Set fence pointer lea initvocl(PC),a2 move.l uvocl(a4),(a2) ; Set vocabulary link lea initLast(PC),a2 move.l ulatest(a4),(a2) ; Set latest NFA ; Now we can read the dictionary into the memory. subi.l #headlen,d1 ; Size of dictionary to read move.l d1,IoReqCount(a0) clr.l IoPosMode(a0) ; Position to beginning of file move.l #headlen,IoPosOffset(a0) ; Offset by headlen _read ; read the dictionary tst.w IoResult(a0) ; Check for errors beq load070 ; continue if ok movea.l IoResult(a0),a0 ; error code loaderror lea userror(PC),a2 move.l a0,(a2) ; Save error code for cold bra.s load080 load070 movea.l a1,a0 ; fcb again _close ; Close the file load080 rts ; -------------------------------------- ; area for calls to Toolbox, etc. ftwork DEFS 20 ftwork1 DC.L 0 dsmsg STR "Parameter Stack:" rsmsg STR "Return Stack: " msmsg STR "Methods Stack: " emptymsg STR " " pausemsg STR "Paused - to continue>>>" bytesleft STR "Bytes Available: " hello STR "Macintosh Yerk Version 3.6.4" ADJST tibbuf DEFS 128 ; terminal input buffer DATA /0 DEFS 20 ; for numeric output padbuf DEFS 256 ; text output buffer aregn DATA 0 ; region handle for miscellany ADJST ; Begin nucleus definitions ADJST cld1 cfas xcold,quit ; do COLD word and enter Forth ; ==================================================== ; Following are data areas that will be patched to look like objects ; after the Class/Object support code is in. Cfas will be patched to ; Class pointers. ; ==================================================== dcode FWIND,x,origin,fwind ; link should be 0 wRecord DEFS windowsize ; window record DC.W 0,0,290,494 ; content rect boundaries DC.W 8,8,340,510 ; grow rect boundaries DC.W -10000,-10000,10000,10000 ; drag rect boundaries DC.W 1,1,1 ; growflg,dragflg, alive DATA nulw-origin ; idle vector DATA cls-origin ; deact vector DATA nulw-origin ; content vector DATA nulw-origin ; draw vector DATA nulw-origin ; enact vector DATA nulw-origin ; close vector DC.W $100 ; resid DC.W 1 ; is this window scrollable? DATA 0 ; special zoom cfa dcode FEVENT,x,fwind,fevent eventRec DC.W 0 ; event record for GetNextEvent eventMsg DC.L 0,0,0 eventMod DC.W 0 eventmsk DC.W 0 eventSlp DC.L 0 mousRgn DC.L 0 DC.W 4,23 ; header for event indexed area DEFS 4*23 dcode FFCB,x,fevent,ffcb ; ------------- Default FCB ------------ useFCB DEFS 144 ; Parm block for USING file useFname DEFS 64 ; holds USING volume/file name string ; ----------------------------------------- fcbl EQU *-useFCB ; length of FCB dcode FPRECT,x,ffcb,fprect pRect DC.W 0,0,294,470 ; Forth window rectangle ; ============================================================= dcode ADOC,x,fprect,adoc jsr loadcom(PC) ; load user dict according to fInfo gonext ; system values dval S0,adoc,s0,0 dval R0,S0,r0,0 dval TIB,r0,tib,tibbuf-origin dval WARNING,tib,warn,1 dval FENCE,warn,fence,0 dval DP,fence,dp,0 dval VOC-LINK,dp,vocl,0 dval IN,vocl,in,0 dval OUT,in,out,0 dval CONTEXT,out,contxt,0 dval CURRENT,contxt,currnt,0 dval STATE,currnt,state,0 dval CSTATE,state,cstate,0 dval BASE,cstate,base,10 dval DPL,base,dpl,0 dval CSP,dpl,csp,0 dval HLD,csp,hld,0 dval WNEAVAIL,hld,wneavail,0 ; true if waitNextEvent in ROM dval HWPAVAIL,wneavail,hwpavail,0 ; true if flush cache dval HASGESTALT,hwpavail,hasGestalt,0 ; true if gestalt is in system dval HEAPTOP,hasGestalt,heapTop,0 ; top of heap filled at start dval HEAPBOT,heapTop,heapBot,0 ; bottom of heap filled at start dval UCASE,heapBot,ucase,1 ; flag for lowercase interpreting dval DOCS,ucase,docs,0 ; flag for document sources loaded dval LINE#,docs,line_,-1 ; line# in source file for documenation dvect VMODEL,line_,vmodel,nulw ; model for other vectors dcon FILEMK,vmodel,filemk,-300+origin ; file mark constant dcon NEXT,filemk,next,donext dcon BEGIN-DP,next,bdp,userdp ; use @ dcon LOAD-ERROR,bdp,lerror,Userror ; use @ dval M0,lerror,m0,0 dcon USE-FCB,m0,ufcb,useFCB ; pushes addr of useFCB dcon MSIZE,ufcb,msiz,memsize ; use @ dcon BL,msiz,bl,$20+origin dcon TRUE,bl,true,1+origin dcon FALSE,true,false,0+origin dsvect KEYVEC,false,keyvec,4,key_ ; system vectors for I/O dsvect EMITVEC,keyvec,emitvec,8,emit_ ; console emit dsvect PEMITVEC,emitvec,pemitv,12,drop ; printer emit dsvect TYPEVEC,pemitv,typevec,16,type_ ; console type dsvect PTYPEVEC,typevec,ptypev,20,drop2 dsvect EXPVEC,ptypev,expvec,24,expect ; expect dsvect ECHOVEC,expvec,echovec,28,emit_ ; echo for keys dsvect ABORTVEC,echovec,abvec,32,nulw ; installable abo dsvect QUITVEC,abvec,quvec,36,nulw ; installable startup vector dsvect UFIND,quvec,ufind,40,false ; vector for user find dsvect OBJINIT,ufind,objini,44,nulw ; init nucleus objs dsvect PCRVEC,objini,pcrvec,48,nulw ; printer CR dsvect BLDVEC,pcrvec,bldvec,52,nulw ; object builder dsvect CREATE,bldvec,kreate,56,creat_ ; create vector dsvect INTERPRET,kreate,interp,60,intrp_ dsvect CRVEC,interp,crvec,64,cr_ dval DISK-ERROR,crvec,dkerr,0 dval CURS,dkerr,curs_,1 ; cursor on/off flag crsflag EQU *-4 dval UCFLAG,curs_,ucflag,1 ; map to upper case ; ============================================== dcode BYE,x,ucflag,bye_ _exitToShell * dcode (CODEZONE),x,bye_,instal lea segStart(PC),a1 ; set CODE 2 resource size movea.l a1,a0 _recoverHandle ; get a handle to appl *** need to unlock move.l (a7)+,d0 ; get ending rel addr addq.l #1,d0 andi.l #-2,d0 ; ensure even addi.l #4,d0 ; add CODE pointer length _SetHandleSize ; increase the size gonext * dcode FINFO,x,instal,finfo ; point to finder handle movea.l f.handle(a5),a0 movea.l (a0),a0 ; dereference suba.l a3,a0 ; make relative move.l a0,-(SP) ; push dereferenced ptr gonext * dcode .CUR,x,finfo,dotcur ; draw a cursor jsr pcurs(PC) gonext * pcurs lea crsflag(PC),a0 ; ( -- ) tst.l (a0) ; is cursor on or off? beq nocurs pea ftwork(PC) _GetPenState ; get the current pen state move.w #10,-(SP) ; set xor mode _PenMode move.w #7,-(SP) clr.w -(SP) _Line pea ftwork(PC) _SetPenState nocurs rts * dcode (EMIT),x,dotcur,emit_ jsr pcurs(PC) addq.l #2,SP ; long -> integer _DrawChar ; expects Pascal CHAR on stack jsr pcurs(PC) gonext * dcode (TYPE),x,emit_,type_ move.l a3,d0 add.l d0,4(SP) ; make address absolute clr.l d0 move.w 2(SP),d0 swap d0 move.l d0,(SP) ; zero start byte offset _DrawText jsr pcurs(PC) gonext * dcode NULW,x,type_,nulw ; empty word for stubbing vectors gonext * dcode WORD0,x,nulw,word0 ; push a word of 0 for function setup clr.w -(SP) gonext * dcode PACK,x,word0,pack_ ; packs 2 longs into one popd0 ; get y addq.l #2,SP move.w d0,-(SP) gonext * dcode UNPACK,x,pack_,unpack move.l (sp),d0 move.w d0,d1 ext.l d1 move.l d1,(SP) asr.l #8,d0 asr.l #8,d0 move.l d0,-(SP) gonext * dcode I->L,x,unpack,itol ; extend 16 bit stack cell to 32 move.w (sp)+,d0 ext.l d0 move.l d0,-(SP) gonext * dcode MAKEINT,x,itol,makint addq.l #2,SP ; drop high-level word on stack gonext * dcode NEWPTR,x,makint,xnewpt popd0 ; get size for new block in d0 _NewPtrC ; call the memory manager for a new block sub.l a3,a0 ; make ptr relative move.l a0,-(SP) ; push ptr to nonrelocatable block gonext * dcode NEWHANDLE,x,xnewpt,xnewha popd0 _newHandC ; special vers of _NewHandle move.l a0,-(SP) ; push handle to relocatable block gonext * * ( hndl -- b) dcode ?ISHANDLE,x,xnewha,ishand movea.l (sp),a0 ; get hndl move.l a0,d0 ; make copy for compares btst #0,d0 ; not hndl if odd bne.s no sub.l a3,d0 ; into yerk mem space cmp.l heapBot9-origin(a3),d0 ; is hndl in prgm heap blt.s no ; not hndl if < bot cmp.l heapTop9-origin(a3),d0 bgt.s no ; not hndl if > top move.l (a0),d0 ; get pointer btst #0,d0 ; not hndl if ptr odd bne.s no move.l d0,d1 ; save ptr copy sub.l a3,d1 ; into yerk mem space cmp.l heapBot9-origin(a3),d1 ; is ptr in prgm heap blt.s no ; not if < bot cmp.l heapTop9-origin(a3),d1 bgt.s no ; not if > top movea.l a0,a1 ; copy hndl movea.l d0,a0 ; move ptr into a0 _recoverHandle cmp.l a0,a1 ; are hndls equal bne.s no moveq #1,d0 ; set true flag bra.s yes no moveq #0,d0 ; set false flag yes move.l d0,(sp) gonext * dcode LOCK,x,ishand,xlock movea.l (SP),a0 ; get handle in a0 _hLock ; mark the block locked movea.l (SP),a0 movea.l (a0),a1 ; dereference the handle suba.l a3,a1 ; make it a Forth address based on a3 move.l a1,(SP) ; leave Forth address on stack gonext * dcode KILLPTR,x,xlock,killpt ; (relPtr -- ) movea.l (SP)+,a0 ; get rel ptr in a0 add.l a3,a0 ; make it absolute _disposPtr ; release it gonext * dcode KILLHANDLE,x,killpt,killha movea.l (SP)+,a0 ; get handle _disposHandle gonext * dcode GROWPTR,x,killha,groptr ; ( bytes relptr --) movea.l (SP)+,a0 ; get rel ptr in a0 adda.l a3,a0 ; make it absolute move.l a0,d4 _getPtrSize add.l (sp)+,d0 ; get new handle size movea.l d4,a0 _SetPtrSize ; grow the block gonext * dcode FREE,x,groPtr,free_ ; ( -- maxAvail ) _freeMem ; what is max mem avail on heap? pushd0 ; includes purging gonext * dcode FREEBLK,x,free_,freblk _maxmem ; what is max mem avail on heap? pushd0 ; includes purging gonext * dcode >PTR,x,freblk,fetptr ; ( handle --- relptr ) movea.l (SP),a0 move.l (a0),d0 ; dereference a handle tst.b wneavail9+3-origin(a3) ; if wne, then stripaddr beq.s noStrip _stripAddress bra.s onPtr noStrip and.l lo3bytes,d0 onPtr sub.l a3,d0 move.l d0,(SP) ; return its pointer gonext * dcode GET-EVENT,x,fetptr,getevt move.l (SP)+,d7 ; get event mask into d7 swap d7 ev1 move.l d7,-(SP) ; make room for function return lea eventRec(PC),a0 ; ptr to event rec storage move.l a0,-(sp) tst.b wneavail9+3-origin(a3) ; is waitnextevent here? beq.s usegne0 move.l 18(a0),-(sp) ; get sleep value move.l 22(a0),-(sp) ; get mouse rgn _waitNextEvt bra.s endevt0 usegne0 _SystemTask ; WNE not in ROM _GetNextEvent endevt0 tst.w (SP)+ ; should we handle this event? beq ev1 ; no - get another one lea eventRec(PC),a0 clr.l d0 move.w (a0),d0 ; pick up event type beq.s ev1 ; loop if null event pushd0 ; push event type for caller gonext * dcode ?EVENT,x,getevt,qevt move.l (SP)+,d7 ; get event mask into d0 swap d7 move.l d7,-(SP) ; make room for function return pea eventRec(PC) ; pointer to event rec storage _EventAvail ; call Toolbox tst.w (SP)+ ; should we handle this event? beq event1 ; no - return false lea eventRec(PC),a0 clr.l d0 move.w (a0),d0 ; pick up event type beq event1 ; loop if null event event2 move.l #1,-(SP) ; push true - event available bra.s event3 event1 clr.l -(SP) ; push false - no event available event3 gonext * dcode GETEVENT,x,qevt,gevt ; ( --- b ) clr.w -(sp) ; make room for function return lea eventRec(PC),a0 move.w eventMsk-eventRec(a0),-(sp) ; get event mask move.l a0,-(sp) tst.b wneavail9+3-origin(a3) ; is waitnextevent here? beq.s usegne move.l 18(a0),-(sp) ; get sleep value move.l 22(a0),-(sp) ; get mouse rgn _waitNextEvt bra.s endevt usegne _SystemTask ; WNE not in ROM _GetNextEvent endevt clr.w -(SP) ; make an integer a long gonext * dcode @EVENT-MSG,x,gevt,ftemsg lea eventMsg(PC),a0 move.l (a0),-(SP) ; push contents of last event msg gonext * ; Flush the caches on 030,040 machines dcode CFLUSH,x,ftemsg,cflush tst.b hwpavail9+3-origin(a3) beq.s noflush moveq #1,d0 _HWPriv noflush gonext * ; FIND-WINDOW ( point -- region, wptr ) dcode FIND-WINDOW,x,cflush,findw popd0 clr.w -(SP) pushd0 pea ftwork1(PC) _FindWindow clr.w -(SP) lea ftwork1(PC),a0 move.l (a0),d0 sub.l a3,d0 pushd0 gonext * dcode INIT-TOOLS,x,findw,intool _InitFonts move.l #$ffff,d0 ; every event rfl 10/89 _FlushEvents _InitWindows _TEInit pea EWRM(PC) ; warm start for Resume button ;in deep shit _InitDialogs clr.l -(SP) ; for windowPtr return move.w #256,-(SP) ; window ID pea wrecord(PC) move.l #-1,-(SP) ; POINTER(-1) for front window _GetNewWindow ; get window resource def _setPort ; setPort(WindowPtr) lea wrecord(PC),a0 move.w #9,txSize(a0) ; window text size = 9 move.w #4,txfont(a0) ; window text font lea pRect(PC),a1 move.l portRect(a0),(a1) move.l portRect+4(a0),4(a1) clr.l -(SP) _NewRgn lea aRegn(PC),a0 move.l (SP)+,(a0) ; fill in region handle clr.w -(SP) _TextMode ; source copy text mode _Initmenus _InitCursor move.w #$9f,d0 ; check for trap availability _getTrapAddress+$600 move.l a0,d3 ; d3 = unimplemented trap addr moveq #$60,d0 ; check for WaitNextEvent _getTrapAddress+$600 cmp.l a0,d3 ; if <> waitnextevent is avail sne d0 move.b d0,wneavail9+3-origin(a3) move.l #$198,d0 ; hwpriv trap addr _getTrapAddress+$200 cmp.l a0,d3 ; if <> hwpriv is avail sne d0 move.b d0,hwpavail9+3-origin(a3) move.l #$1ad,d0 ; gestalt avail _getTrapAddress+$200 cmp.l a0,d3 sne d0 move.b d0,hasGestalt9+3-origin(a3) move.l heapend,d0 sub.l a3,d0 move.l d0,heapTop9-origin(a3) move.l applzone,d0 sub.l a3,d0 move.l d0,heapBot9-origin(a3) gonext * dcode HOME,x,intool,home dohome move.l #$f0008,d0 pushd0 _MoveTo ; home gonext * dcode CLS,x,home,cls pea pRect(PC) _EraseRect jmp dohome(PC) gonext * dcode SCROLL,x,cls,scroll ; (dh dv --- ) popd0 popd1 pea pRect(PC) move.w d1,-(SP) move.w d0,-(SP) lea aregn(PC),a0 ; get dummy region handle move.l (a0),-(SP) _ScrollRect gonext * dcode >ORIGIN,x,scroll,setorg popd0 addq.l #2,SP move.w d0,-(SP) _SetOrigin gonext * dcode LINE,x,setorg,xline ; (dh dv ---) popd0 addq.l #2,SP move.w d0,-(SP) _Line gonext * dcode LINETO,x,xline,xline2 ; (x y --) popd0 addq.l #2,SP move.w d0,-(sp) _LineTo gonext * dcode LIT,x,xline2,lit ; build code header move.l (a4)+,-(SP) ; push value at IP to stack gonext * dcode WLIT,x,lit,wlit ; build code header move.w (a4)+,-(SP) ; push value at IP to stack clr.w -(SP) ; extend to 32 bits gonext * dcode WLITW,x,wlit,wlitw ; build code header move.w (a4)+,-(sp) ; push value at IP to stack gonext ; no extend * dcode W@(IP),x,wlitw,wfetip move.l (a6),d0 ; get IP from 1 nest back move.w 0(a3,d0.l),-(SP) ; push the word clr.w -(SP) add.l #2,(a6) ; increment old IP past word gonext * dcode EXECUTE,x,wfetip,exec move.l (SP)+,d6 ; pop address to execute move.l 0(a3,d6.l),d7 ; get contents of CFA jmp 0(a3,d7.l) ; execute the code * dcode TRAP,x,exec,trap_ ; execute passed-in Tool trap popD0 ; get trap in d0 lea trapword(PC),a0 move.w d0,(a0) ; store trap inline for execution tst.b hwpavail9+3-origin(a3) beq.s trapword ; don't flush if hwpriv unavail moveq #1,d0 ; flush the cache on 030,040 _HWPriv nop ; so we don't get burned by prefetch trapword DC.W $A997 ; start with openresfile gonext * dcode (GESTALT),x,trap_,gestalt_ moveq #-1,d0 move.b hasGestalt9+3-origin(a3),d1 beq nogest move.l (sp),d0 clr.l d1 move.l d1,a0 _gestalt move.l a0,(sp) ext.l d0 bmi.s nogest moveq #0,d0 bra.s isgest nogest addq #4,sp isgest move.l d0,-(sp) gonext * dcode GOTOXY,x,gestalt_,gotoxy popd0 ; get Y in d0 addq.l #2,SP ; drop high-level word on stack move.w d0,-(SP) _MoveTo ; call Quickdraw to move pen gonext * dcode BEEP,x,gotoxy,beep ; ( dur -- ) addq.l #2,sp _sysbeep gonext * dcode @XY,x,beep,fetxy ; return X,Y pen location pea ftwork(PC) _GetPen lea ftwork(PC),a0 clr.l d0 move.w 2(a0),d0 pushd0 ; push X value move.w (a0),d0 pushd0 ; push Y value gonext * dcode BRANCH,x,fetxy,bran adda.l (a4),a4 ; add relative offset to IP gonext * dcode 0BRANCH,x,bran,bran0 move.l (SP)+,d0 ; pop data stack into d0 bne br1 ; if non-0, ignore branch following adda.l (a4),a4 ; else take the branch bra.s br2 br1 addq.l #4,a4 ; next 32-bit cfa br2 gonext * dcode OFBR,x,bran0,ofbr ; 0branch used by OF clauses move.l (SP)+,d0 ; pop data stack into d0 bne ofbr1 ; if non-0, ignore branch move.l (a6),d1 ; get IP from return stack move.l 0(a3,d1.l),d2 add.l d2,(a6) ; add to stacked IP bra.s ofbr2 ofbr1 addq.l #4,(a6) ; next 32-bit cfa 1 nest back addq.l #4,SP ; drop the value ofbr2 gonext * dcode FAKE,x,ofbr,fake_ ; use as a breakpoint with debugg jmp *(PC) gonext * dcode (LOOP),x,fake_,loop_ ; (loop) addq.l #1,(a6) ; bump index (long) move.l (a6),d0 cmp.l 4(a6),d0 ; compare index to limit bge xloop1 adda.l (a4),a4 ; branch back to top of loop gonext xloop1 addq.l #8,a6 ; pop index,limit from return stack addq.l #4,a4 gonext * dcode (DO),x,loop_,do_ ; this DO terminates on limit=count move.l (SP),d0 cmp.l 4(SP),d0 ; does limit=count? if so, terminate bne doloop adda.l (a4),a4 ; forward jump IP addq.l #8,SP gonext doloop move.l 4(SP),-(a6) ; limit val to Return stack move.l d0,-(a6) ; start val addq.l #4,a4 ; skip the jump addr addq.l #8,SP gonext * dcode (LOOP+),x,do_,ploop_ move.l (SP)+,d0 bmi xploop1 add.l d0,(a6) move.l (a6),d0 cmp.l 4(a6),d0 bge xploop2 adda.l (a4),a4 bra.s xploop3 xploop1 add.l D0,(a6) move.l (a6),d0 cmp.l 4(a6),d0 ble xploop2 adda.l (a4),a4 bra.s xploop3 xploop2 addq.l #8,a6 addq.l #4,a4 xploop3 gonext * dcode I,x,ploop_,i move.l (a6),-(SP) gonext * dcode I+,x,i,iplus ; add I to top of stack move.l (a6),d0 add.l d0,(SP) gonext * dcode I-,x,iplus,iminus move.l (a6),d0 sub.l d0,(SP) gonext * dcode I@,x,iminus,ifetch ; fetch from I as addr move.l (A6),d7 move.l 0(a3,d7.l),-(sp) gonext * dcode I!,x,ifetch,istore move.l (A6),d7 move.l (SP)+,0(a3,d7.l) gonext * dcode IC@,x,istore,icfet clr.l d0 move.l (a6),d7 move.b 0(a3,d7.l),d0 move.l d0,-(SP) gonext * dcode IC!,x,icfet,icstor move.l (A6),d7 move.l (sp)+,d0 move.b d0,0(a3,d7.l) gonext * dcode J,x,icstor,j move.l 8(a6),-(SP) gonext * dcode DIGIT,x,j,digit popd0 popd1 clr.l d2 subi.l #$30,d1 bmi dig2 cmpi.l #$0a,d1 bmi dig1 subq.l #7,d1 cmpi.l #$0a,d1 ; to fix FIG bug that lets 58-64 pass bmi dig2 dig1 cmp.l d0,d1 bge dig2 moveq #1,d2 pushd1 dig2 pushd2 gonext * dcode TRAVERSE,x,digit,traver popd0 popd1 moveq #$20,d2 lea 0(a3,d1.l),a0 tst.l d0 bmi trav1 move.b (a0),d0 andi.l #$1f,d0 adda.l d0,a0 move.l a0,d0 andi.l #1,d0 suba.l d0,a0 addq.l #1,a0 bra.s trav2 trav1 tst.b (a0) bmi trav2 subq.l #1,d2 ; exit early if drags on beq trav2 subq.l #1,a0 bra.s trav1 trav2 suba.l a3,a0 move.l a0,-(SP) gonext * dcode (FIND),x,traver,find_ clr.l d1 move.l (SP)+,d7 lea 0(a3,d7.l),a0 pfind1 movea.l a0,a2 move.l (SP),d7 lea 0(a3,d7.l),a1 move.b (a2)+,d1 andi.l #$03f,d1 cmp.b (a1)+,d1 bne pfind3 move.l d1,d0 pfind2 cmpm.b (a1)+,(a2)+ bne pfind3 subq.l #1,d0 bne.s pfind2 bsr odd addq.l #8,a2 suba.l a3,a2 move.l a2,(SP) move.b (a0),d0 pushD0 moveq #1,d0 bra.s pfind4 pfind3 movea.l a0,a2 andi.w #$1f,d1 adda.l d1,a2 addq.l #1,a2 bsr odd move.l (a2),d7 lea 0(a3,d7.l),a0 tst.l (a2) bne.s pfind1 addq.l #4,SP clr.l d0 pfind4 pushD0 gonext odd move.l a2,d0 moveq #1,d1 and.l d1,d0 adda.l d0,a2 rts * ; ( SelPfa ^class -- f OR 1cfa t) dcode ((FINDM)),x,find_,findm_ move.l (SP)+,d7 ; get relative ^class move.l (SP)+,d0 ; get SelPfa to match move.l 0(a3,d7.l),d7 ; get contents of ^methods link field findm0 lea 0(a3,d7.l),a1 ; get absolute ^methods dict nfa findm1 cmp.w (a1),d0 ; is this the method we want? beq foundm ; yes, we found the method move.l 2(a1),d7 ; link to previous method entry beq notfndm ; end of methods dict - not found bra.s findm0 foundm addi.l #10,d7 ; point to 1cfa of method move.l d7,-(SP) ; push 1cfa to stack move.l #1,-(SP) ; true bra.s fmexit ; return to Forth notFndm clr.l -(SP) fmexit gonext * * ( addr delim -- addr n1 n2 n3 ) dcode ENCLOSE,x,findm_,enclos popd0 ; get delim in d0 move.l (SP),d7 ; addr in d7 lea 0(a3,d7.l),a0 ; a0 has abs addr clr.l d1 encGet move.b (a0)+,d2 ; get next byte in d2 beq encNull ; null - unconditional exit cmpi.b #9,d2 ; is char a Tab? bne notab1 move.b #32,d2 ; map tabs to spaces notab1 cmp.b d0,d2 ; does first char = delim? bne encNext ; no addq.l #1,d1 ; get another char bra.s encGet encNull pushd1 ; found null- push idx at null addq.l #1,d1 ; push idx of byte following pushd1 bra.s encl5 ; exit encNext pushd1 ; idx of first non-delim subq.l #1,a0 encl3 move.b (a0)+,d2 beq encl4 cmp.b #9,d2 ; is char a Tab? bne notab2 move.b #32,d2 ; map tabs to spaces notab2 cmp.b d0,d2 beq encl4 addq.l #1,d1 bra.s encl3 encl4 move.l d1,-(SP) tst.b d2 beq encl5 addq.l #1,d1 encl5 pushd1 ; push unexamined idx and leave gonext * dcode (S=),x,enclos,sequ_ ; ( addr addr len -- b) popd0 ; get length of string comparison subq.l #1,d0 ; setup counter for dbeq movea.l (SP)+,a0 movea.l (SP)+,a1 adda.l a3,a0 adda.l a3,a1 dosequ cmpm.b (a0)+,(a1)+ dbne d0,dosequ cmp.w #-1,d0 beq xsequ ; counter was exhausted, so true clr.l -(SP) ; push false bra.s nextsequ xsequ move.l #1,-(SP) ; push true nextsequ gonext * dcode CMOVE,x,sequ_,cmove docmove move.l (SP)+,d0 movea.l (SP)+,a1 movea.l (SP)+,a0 adda.l a3,a0 adda.l a3,a1 cmov1 _BlockMove gonext * ; the somewhat dreaded multiply routines mpy move.l (SP)+,-(a6) ; save return address from jsr tst.w (SP) ; try short multiply first bne mpy1 tst.w 4(SP) ; if both high words=0, we bne mpy1 ; can do a short multiply popd0 popd1 mulu d0,d1 pushd1 clr.l d1 pushd1 move.l (a6)+,-(SP) rts mpy1 popd0 ; this is long multiply popd1 moveq #0,d2 move.l d2,-(SP) move.l d2,-(SP) move.w d1,d2 mulu d0,d2 move.l d2,4(SP) move.l d1,d2 swap d2 mulu d0,d2 add.l d2,2(SP) swap d0 move.w d1,d2 mulu d0,d2 add.l d2,2(SP) bcc mpy2 addq.w #1,(SP) mpy2 move.l d1,d2 swap d2 mulu d0,d2 add.l d2,(SP) move.l (a6)+,-(SP) rts smpy move.l (SP)+,-(a6) tst.l (SP) ; signed multiply smi d4 bpl smpy1 neg.l (SP) smpy1 tst.l 4(SP) smi d3 bpl smpy2 neg.l 4(SP) smpy2 eor.b d3,d4 bsr.s mpy tst.b d4 beq smpy3 neg.l 4(SP) negx.l (SP) smpy3 move.l (a6)+,-(SP) rts xdiv move.l (SP)+,-(a6) tst.l (SP) beq div5 tst.w (SP) bne longdiv tst.l 4(SP) bne longdiv move.l (SP)+,d2 popd0 popd1 divu d2,d1 bvs long1 clr.l d2 move.w d1,d2 clr.w d1 swap d1 pushd1 move.l d2,-(SP) move.l (a6)+,-(SP) rts longdiv move.l (SP)+,d2 ; the dreaded long division popd0 popd1 long1 moveq #32,d3 sub.l d2,d0 div1 bmi div2 ori.l #1,d1 subq.w #1,d3 bmi div3 asl.l #1,d1 roxl.l #1,d0 sub.l d2,d0 bra.s div1 div2 subq.w #1,d3 bmi div3 asl.l #1,d1 roxl.l #1,d0 add.l d2,d0 bra.s div1 div3 tst.l d0 bpl div4 add.l d2,d0 div4 pushd0 pushd1 move.l (a6)+,-(SP) rts div5 addq.l #4,SP move.l d2,4(SP) move.l #$7fffffff,(SP) move.l (a6)+,-(SP) rts sdiv move.l (SP)+,-(a6) ; save return address from jsr tst.l (SP) ; signed divide smi d7 ; d4 change to d7 8-24-91 bpl sdiv1 neg.l (SP) sdiv1 tst.l 4(SP) smi d4 ; d7 changed to d4 to let rem sign = quotient sign bpl sdiv2 neg.l 8(SP) negx.l 4(SP) sdiv2 eor.b d4,d7 bsr xdiv tst.b d7 beq sdiv3 neg.l (SP) sdiv3 tst.b d4 beq sdiv4 neg.l 4(SP) sdiv4 move.l (a6)+,-(SP) rts slmod move.l (SP)+,-(a6) moveq #0,d1 popd0 tst.l (SP) bpl slmod1 subq.l #1,d1 slmod1 pushd1 pushd0 move.l (a6)+,-(SP) bra.s sdiv * dcode U*,x,cmove,ustar bsr mpy gonext * dcode U/,x,ustar,uslash bsr xdiv gonext * dcode M*,x,uslash,mstar bsr smpy gonext * dcode M/,x,mstar,mslash bsr sdiv gonext * dcode */,x,mslash,starsla move.l (SP)+,-(a6) bsr smpy move.l (a6)+,-(SP) bsr sdiv move.l (SP)+,(SP) gonext * dcode */MOD,x,starsla,ssmod move.l (SP)+,-(a6) bsr smpy move.l (a6)+,-(SP) bsr sdiv gonext * dcode M/MOD,x,ssmod,msmod move.l (SP)+,-(a6) moveq #0,d0 pushd0 move.l (a6),-(SP) bsr xdiv move.l (a6)+,d0 move.l (SP)+,-(a6) pushd0 bsr xdiv move.l (a6)+,-(SP) gonext * dcode *,x,msmod,star ; * bsr smpy addq.l #4,SP ; drop top of stack gonext * dcode /,x,star,slash ; / bsr slmod move.l (SP)+,(SP) gonext * dcode /MOD,x,slash,xslmod ; /MOD bsr slmod gonext * dcode MOD,x,xslmod,mod ; MOD bsr slmod addq.l #4,SP gonext * dcode D>,x,mod,dgrt ; D> moveq #1,d0 move.l 8(SP),d1 cmp.l (SP),d1 bgt dgrt1 move.l 12(SP),d1 cmp.l 4(SP),d1 bgt dgrt1 moveq #0,d0 dgrt1 adda.l #16,SP pushd0 gonext * dcode D<,x,dgrt,dless ; D< moveq #1,d0 move.l 8(SP),d1 cmp.l (SP),d1 blt dless1 move.l 12(SP),d1 cmp.l 4(SP),d1 blt dless1 moveq #0,d0 dless1 adda.l #16,SP pushd0 gonext * dcode D=,x,dless,dequ ; D= move.l (SP),d1 cmp.l 8(SP),d1 seq d0 move.l 4(SP),d1 cmp.l 12(SP),d1 seq d1 adda.l #16,SP and.l d1,d0 bra setbyt gonext * dcode U<,x,dequ,uless cmp2 scs d0 bra.s setbyt * dcode U>,x,uless,ugrt cmp2 scc d0 bra.s setbyt * dcode <,x,ugrt,less ; < cmp2 slt d0 bra.s setbyt * dcode >,x,less,grt ; > cmp2 sgt d0 bra.s setbyt * dcode =,x,grt,equals ; = cmp2 seq d0 bra.s setbyt * dcode <>,x,equals,nequals cmp2 sne d0 bra.s setbyt * dcode 0=,x,nequals,zequ tst.l (SP)+ seq d0 bra.s setbyt * dcode 0<,x,zequ,zless tst.l (SP)+ smi d0 setbyt moveq #1,d1 and.l d1,d0 pushD0 gonext * dcode 0>,x,zless,zgrt tst.l (SP)+ sgt d0 bra.s setbyt * dcode <=,x,zgrt,lesequ cmp2 sle d0 bra.s setbyt * dcode >=,x,lesequ,grtequ cmp2 sge d0 bra.s setbyt * dcode 0!,x,grtequ,zstore ; store 0 at addr move.l (sp)+,d7 clr.l 0(a3,d7.l) gonext * dcode 0,x,zstore,pzer ; short, fast 0 word clr.l -(SP) gonext * dcode 1,x,pzer,pone ; short, fast 1 word move.l #1,-(SP) gonext * dcode -1,x,pone,pmone ; short, fast -1 word move.l #-1,-(SP) gonext * dcode 2,x,pmone,ptwo ; short, fast 2 word move.l #2,-(SP) gonext * dcode 4,x,ptwo,pfour move.l #4,-(SP) gonext * dcode AND,x,pfour,and_ popD0 and.l d0,(SP) gonext * dcode LAND,x,and_,land_ popd0 tst.l (SP) beq land2 move.l #1,(SP) tst.l d0 beq land1 moveq #1,d0 land1 and.l d0,(SP) land2 gonext * dcode OR,x,land_,or_ popD0 or.l d0,(SP) gonext * dcode LOR,x,or_,lor_ popd0 tst.l d0 beq lor1 moveq #1,d0 lor1 tst.l (SP) beq lor2 move.l #1,(SP) lor2 or.l d0,(SP) gonext * dcode XOR,x,lor_,xor popD0 eor.l d0,(SP) gonext * dcode LXOR,x,xor,lxor popd0 tst.l d0 beq lxor1 moveq #1,d0 lxor1 tst.l (SP) beq lxor2 move.l #1,(SP) lxor2 eor.l d0,(SP) gonext * dcode HERE,x,lxor,here move.l #(dp9-origin),d7 move.l 0(a3,d7.l),-(SP) gonext * dcode ALLOT,x,here,allot move.l #(dp9-origin),d7 popD0 add.l d0,0(a3,d7.l) ; increment DP gonext * dcode SP@,x,allot,spfet move.l SP,d0 sub.l a3,d0 pushD0 gonext * dcode SP!,x,spfet,spstor move.l #(s09-origin),d7 move.l 0(a3,d7.l),d7 lea 0(a3,d7.l),SP ; add a3 to it and store in SP gonext * dcode RP@,x,spstor,rpfet move.l a6,d0 sub.l a3,d0 pushD0 gonext * dcode RP!,x,rpfet,rpstor move.l #(r09-origin),d7 move.l 0(a3,d7.l),d7 lea 0(a3,d7.l),a6 ; add a3 to it and store in RP gonext * dcode MP!,x,rpstor,mpstor move.l initmp(PC),d5 add.l a3,d5 ; get initmp and add a3 to it gonext * dcode MP@,x,mpstor,mpfet move.l d5,d0 sub.l a3,d0 pushD0 gonext * dcode THEPORT,x,mpfet,port_ move.l (a5),a0 ; Point to QD globals move.l (a0),d0 ; point to current grafport sub.l a3,d0 pushd0 gonext * dcode (LCWORD),x,port_,lcword ; doesn't map to upper ca popd0 ; d0=len to next word lea in9(PC),a0 add.l d0,(a0) ; bump IN popd0 ; d0=offs to end of parsed word popd1 ; d1=offs to beg of parsed word sub.w d1,d0 ; d0=len this word lea dp9(PC),a0 movea.l (a0),a0 ; a0=relative DP adda.l a3,a0 ; a0=abs DP = HERE move.b d0,(a0) ; store len move.b #32,1(a0,d0.l) ; blank at end of word movea.l (SP)+,a1 ; addr of string adda.l a3,a1 adda.l d1,a1 ; a1=source address to move from wMov move.b -1(a1,d0.w),0(a0,d0.w) ; copy the string subq.l #1,d0 bne.s wMov gonext * dcode (WORD),x,lcword,word_ ; fast code for WORD popd0 ; d0=len to next word lea in9(PC),a0 add.l d0,(a0) ; bump IN popd0 ; d0=offs to end of parsed word popd1 ; d1=offs to beg of parsed word sub.w d1,d0 ; d0=len this word lea dp9(PC),a0 movea.l (a0),a0 ; a0=relative DP adda.l a3,a0 ; a0=abs DP = HERE move.b d0,(a0) ; store len move.b #32,1(a0,d0.l) ; blank at end of word movea.l (SP)+,a1 ; addr of string adda.l a3,a1 adda.l d1,a1 ; a1=source address to move from wordMov move.b -1(a1,d0.w),0(a0,d0.w) ; copy the string tst.b ucase9+3-origin(a3) ; is upper case flag on? beq.s wordmov1 cmpi.b #96,0(a0,d0.w) ble wordmov1 ; map to upper case cmpi.b #123,0(a0,d0.w) bge wordMov1 subi.b #32,0(a0,d0.w) wordmov1 subq.l #1,d0 bne.s wordMov gonext * dcode (DODO),x,word_,dodo ; code for mcfa words dodo1 move.w -2(a3,d7.l),d0 ; pickup len to child's pfa add.l d0,d6 ; advance wp move.l d6,-(sp) ; push pfa for do> code suba.l a3,a4 move.l a4,-(a6) ; save old IP on RP lea 10(a3,d7.l),a4 ; point IP to threaded code gonext * ; this code gets compiled before each piece of DO.. code (10 bytes long) dcode DOJMP,x,dodo,dojmp move.l #(dodo1-origin),d0 jmp 0(a3,d0.l) * ; this code gets compiled into the front of each class definition ; and is pointed to by the cfa of all objects dcode DOOBJ,x,dojmp,doobj obcode addq.l #4,d6 ; d6->pfa of object dirObj move.l d6,-(SP) ; push obj addr gonext * ; this is the code pointed to by the cfa of all classes dcode DOCLASS,x,doobj,dclass addq.l #4,d6 move.l d6,-(SP) ; push ^class on stack move.l #(bldvec-origin),d6 ; d6 has cfa of BLDVEC move.l 0(a3,d6.l),d7 ; d7 has code addr of BLDVEC jmp 0(a3,d7.l) ; do it * ; runtime code for a message to a public object dcode M0CFA,x,dclass,zcfa movea.l d5,a2 clr.l d0 clr.l d4 move.l (SP)+,d3 ; get obj addr in d3 move.b 8(a3,d6.l),d0 ; pickup #args for named stack beq noArgs addq.l #2,d6 ; skip extra word for #args in method move.l d0,d1 ; save #args lsr.b #4,d0 ; get #temps nybble beq noLocs ; no local vars move.l d0,d4 ; accum total #cells in d4 lsl.b #2,d0 ; compute #bytes = cells*4 suba.l d0,a2 ; allocate temp space noLocs andi.b #$0f,d1 ; low nybble has #input parms beq noIns ; no input parms add.l d1,d4 someArgs move.l (SP)+,-(a2) ; pop data stack to methods stack subq.w #1,d1 bne.s someArgs ; transfer all args from data stack noIns move.l d4,d0 noArgs move.l d0,-(a2) ; push #args to methods stack move.l d3,-(a2) ; d3 has base address of local data move.l a2,d5 suba.l a3,a4 ; Perform colcode move.l a4,-(a6) addq.l #8,d6 lea 0(a3,d6.l),a4 gonext * ; runtime code for a message to a private ivar dcode M1CFA,x,zcfa,onecfa move.l d5,a2 clr.l d0 clr.l d4 move.w (a4)+,d0 ; get offset to ivar bge notSelf ; if negative, this is a Self reference clr.l d0 ; if self, preserve base addr notSelf move.l (a2),d2 ; get base address add.l d0,d2 ; add offset to base address clr.w d0 move.b 4(a3,d6.l),d0 ; pickup #args for named stack beq noArgs1 addq.l #2,d6 ; skip extra word for #args in method move.l d0,d1 ; save #args lsr.b #4,d0 ; get #temps nybble beq nolocs1 move.l D0,D4 ; total #cells lsl.b #2,d0 ; compute #bytes = cells*4 suba.l d0,a2 ; allocate temp space noLocs1 andi.b #$0f,d1 ; low nybble has #input parms beq noins1 add.l d1,d4 ; save #input parms args1 move.l (SP)+,-(a2) ; pop data stack to methods stack subq.w #1,d1 bne.s args1 ; transfer all args from data stack noins1 move.l d4,d0 noArgs1 move.l d0,-(a2) ; push #args to methods stack move.l d2,-(a2) ; push offset+base to mstack mNest move.l a2,d5 suba.l a3,a4 ; do colcode nest move.l a4,-(a6) addq.l #4,d6 lea 0(a3,d6.l),a4 gonext * dcode (;M),x,onecfa,semim_ ; this is the ;m definition addq.l #8,d5 ; pop two entries from mstack movea.l d5,a2 move.l -4(a2),d0 ; look at #args beq noPop lsl.w #2,d0 ; setup to add #args*4 adda.l d0,a2 ; pop #args move.l a2,d5 noPop move.l (a6)+,d7 lea 0(a3,d7.l),a4 gonext * dcode ;S,x,semim_,semis ; this is the ;S definition move.l (a6)+,d7 lea 0(a3,d7.l),a4 gonext * dcode COLP,x,semis,pcolon ; named stack colon code pcolcode move.l d5,a2 clr.l d0 clr.l d4 move.b 4(a3,d6.l),d0 ; pickup #args for named stack beq noArgs3 addq.l #2,d6 ; skip extra word for #args in method move.l d0,d1 ; save #args lsr.b #4,d0 ; get #temps nybble beq noLocs3 ; no local vars move.l d0,d4 ; accum total #cells in d4 lsl.b #2,d0 ; compute #bytes = cells*4 sub.l d0,a2 ; allocate temp space NoLocs3 andi.b #$0f,D1 ; low nybble has #input parms beq noIns3 ; no input parms add.l d1,d4 Args3 move.l (SP)+,-(a2) ; pop data stack to methods stack subq.w #1,d1 bne.s Args3 ; transfer all args from data stack noIns3 move.l d4,d0 noArgs3 move.l d0,-(a2) ; push #args to methods stack clr.l -(a2) ; waste the objaddr cell move.l a2,d5 ; suba.l a3,a4 ; Perform colcode move.l a4,-(a6) addq.l #4,d6 lea 0(a3,d6.l),a4 gonext * dcode (SEMIP),x,pcolon,semip ; named stack denester co addq.l #8,d5 ; pop two entries from mstack movea.l d5,a2 move.l -4(a2),d0 ; look at #args beq noPops1 lsl.w #2,d0 ; setup to add #args*4 adda.l d0,a2 ; pop #args move.l a2,d5 nopops1 move.l (a6)+,d7 lea 0(a3,d7.l),a4 gonext * dcode LEAVE,x,semip,leave move.l (a6),4(a6) gonext * dcode >R,x,leave,toR move.l (SP)+,-(a6) gonext * dcode R>,x,toR,rFrom move.l (a6)+,-(SP) gonext * dcode R,x,rFrom,r move.l (a6),-(SP) gonext * dcode PUSHM,x,r,mpush exg d5,a2 move.l (SP)+,-(a2) exg d5,a2 gonext * dcode POPM,x,mpush,mpop exg d5,a2 move.l (a2)+,-(SP) exg d5,a2 gonext * dcode COPYM,x,mpop,mcopy move.l d5,a2 move.l (a2),-(SP) gonext * dcode EXGM,x,mcopy,mexg exg d5,a2 move.l (SP),d0 move.l (a2),(SP) move.l d0,(a2) gonext * dcode DUPM,x,mexg,mdup dupm exg d5,a2 move.l (a2),-(a2) exg d5,a2 gonext * dcode ADDM,x,mdup,madd popd0 addmd0 exg d5,a2 ; copied this from nucleus--suspect! add.l d0,(a2) exg d5,a2 gonext * dcode DROPM,x,madd,mdrop exg d5,a2 ; *** popmd0 move.l (a2)+,d0 exg d5,a2 gonext * dcode MP0,x,mdrop,mp0 ; mstack picks for named parms move.l d5,a2 move.l 8(a2),-(SP) ; push parm to data stack gonext * dcode MP1,x,mp0,mp1 ; mstack picks for named parms move.l d5,a2 move.l 12(a2),-(SP) ; push parm to data stack gonext * dcode MP2,x,mp1,mp2 ; mstack picks for named parms move.l d5,a2 move.l 16(a2),-(SP) ; push parm to data stack gonext * dcode MP3,x,mp2,mp3 ; mstack picks for named parms move.l d5,a2 move.l 20(a2),-(SP) ; push parm to data stack gonext * dcode MP4,x,mp3,mp4 ; mstack picks for named parms move.l d5,a2 move.l 24(a2),-(SP) ; push parm to data stack gonext * dcode MP5,x,mp4,mp5 ; mstack picks for named parms move.l d5,a2 move.l 28(a2),-(SP) ; push parm to data stack gonext * dcode MS0,x,mp5,ms0 ; mstack stores for named parms move.l d5,a2 move.l (SP)+,8(a2) ; replace parm val with top of stack gonext * dcode MS1,x,ms0,ms1 ; mstack stores for named parms move.l d5,a2 move.l (SP)+,12(a2) ; replace parm val with top of stack gonext * dcode MS2,x,ms1,ms2 ; mstack stores for named parms move.l d5,a2 move.l (SP)+,16(a2) ; replace parm val with top of stack gonext * dcode MS3,x,ms2,ms3 ; mstack stores for named parms move.l d5,a2 move.l (SP)+,20(a2) ; replace parm val with top of stack gonext * dcode MS4,x,ms3,ms4 ; mstack stores for named parms move.l d5,a2 move.l (SP)+,24(a2) ; replace parm val with top of stack gonext * dcode MS5,x,ms4,ms5 ; mstack stores for named parms move.l d5,a2 move.l (SP)+,28(a2) ; replace parm val with top of stack gonext * dcode (++>),x,ms5,minc ; increment named parm move.l d5,a2 move.w (a4)+,d0 ; get element offset move.l (sp)+,d1 ; get increment value add.l d1,0(a2,d0.w) ; increment the cell gonext * dcode (EX>),x,minc,mdo ; execute a procedural arg move.l d5,a2 move.w (a4)+,d0 ; get offset to named parm move.l 0(a2,d0.w),d6 ; get the cfa move.l 0(a3,d6.l),d7 ; get the code jmp 0(a3,d7.l) * dcode +,x,mdo,plus popD0 add.l d0,(SP) gonext * dcode -,x,plus,subt popD0 sub.l d0,(SP) gonext * dcode MAX,x,subt,max popD0 cmp.l (SP),d0 blt maxq move.l d0,(SP) maxq gonext * dcode MIN,x,max,min popD0 cmp.l (SP),d0 bgt minq move.l d0,(SP) minq gonext * dcode NEGATE,x,min,minus mins1 neg.l (SP) gonext * dcode DNEGATE,x,minus,dminus dmins1 neg.l 4(SP) negx.l (SP) gonext * dcode CFA,x,dminus,cfa subq.l #4,(SP) gonext * dcode +-,x,cfa,plmin tst.l (SP)+ bmi.s mins1 gonext * dcode ABS,x,plmin,abs tst.l (SP) bmi.s mins1 gonext * dcode DABS,x,abs,dabs tst.l (SP) bmi.s dmins1 gonext * dcode S->D,x,dabs,sToD moveq #0,d0 tst.l (SP) bpl GOHERE subq.l #1,d0 GOHERE pushd0 gonext * dcode OVER,x,sToD,over move.l 4(SP),-(SP) gonext * dcode 2OVER,x,over,over2 move.l 12(SP),-(SP) move.l 12(SP),-(SP) gonext * dcode DROP,x,over2,drop addq.l #4,SP gonext * dcode 2DROP,x,drop,drop2 addq.l #8,SP gonext * dcode SWAP,x,drop2,swap_ popD0 move.l (SP),d1 move.l d0,(SP) pushD1 gonext * dcode 2SWAP,x,swap_,swap2 popD0 popD1 move.l (SP)+,d3 move.l (SP),d4 move.l d1,(SP) move.l d0,-(SP) move.l d4,-(SP) move.l d3,-(SP) gonext * dcode DUP,x,swap2,dup move.l (SP),-(SP) gonext * dcode 2DUP,x,dup,dup2 move.l 4(SP),-(SP) move.l 4(SP),-(SP) gonext * dcode -DUP,x,dup2,mindup tst.l (SP) beq ddup move.l (SP),-(SP) ddup gonext * dcode +!,x,mindup,plstor move.l (SP)+,d7 popD0 add.l d0,0(a3,d7.l) gonext * dcode TOGGLE,x,plstor,toggle popD0 move.l (SP)+,d7 eor.b d0,0(a3,d7.l) gonext * dcode W@,x,toggle,wfetch ; this is a 16-bit fetch clr.l d0 move.l (SP),d7 move.w 0(a3,d7.l),d0 move.l d0,(SP) gonext * dcode @,x,wfetch,fetch ; this is a 32-bit fetch move.l (SP),d7 move.l 0(a3,d7.l),(SP) gonext * dcode C@,x,fetch,cfetch clr.l d0 move.l (SP),d7 move.b 0(a3,d7.l),d0 move.l d0,(SP) gonext * dcode MW@,x,cfetch,mwfetch ; 16-bit fetch from mstack addr move.l d5,a2 clr.l d0 move.l (a2),d7 move.w 0(a3,d7.l),d0 ext.l d0 ; sign-extend move.l d0,-(SP) gonext * dcode M@,x,mwfetch,mfetch ; this is a 32-bit fetch move.l d5,a2 move.l (a2),d7 move.l 0(a3,d7.l),-(SP) gonext * dcode 2@,x,mfetch,fetch2 ; ( double word fetch ) move.l (SP),d7 lea 0(a3,d7.l),a0 move.l (a0)+,-(sp) move.l (a0),4(SP) gonext * dcode W!,x,fetch2,wstore ; 16-bit store move.l (SP)+,d7 ; address is relative to a3 popD0 ; d0 has value move.w d0,0(a3,d7.l) gonext * dcode W+!,x,wstore,wpstore ; 16-bit plus store move.l (SP)+,d7 popD0 add.w d0,0(a3,d7.l) gonext * dcode !,x,wpstore,store ; 32-bit store move.l (SP)+,d7 ; address is relative to a3 popD0 ; d0 has value move.l d0,0(a3,d7.l) gonext * dcode C!,x,store,cstore move.l (SP)+,d7 popD0 move.b d0,0(a3,d7.l) gonext * dcode C+!,x,cstore,cpstore ; 8 bit plus store move.l (SP)+,d7 popD0 add.b d0,0(a3,d7.l) gonext * dcode MW!,x,cpstore,mwstore ; 16-bit store to addr on mstack move.l d5,a2 move.l (a2),d7 ; address is relative to a3 popD0 ; d0 has value move.w d0,0(a3,d7.l) gonext * dcode M!,x,mwstore,mstore ; 32-bit store to addr on mstack move.l d5,a2 move.l (a2),d7 ; address is relative to a3 popD0 ; d0 has value move.l d0,0(a3,d7.l) gonext * dcode 2!,x,mstore,store2 ; ( double word store ) move.l (SP)+,d7 lea 0(a3,d7.l),a0 move.l (SP)+,(a0)+ move.l (SP)+,(a0) gonext * dcode D+,x,store2,dplus ; 64-bit add popd0 popd1 move.l (SP)+,d2 move.l (sp)+,d3 add.l d1,d3 addx.l d0,d2 move.l d3,-(SP) move.l d2,-(SP) gonext * dcode 1+,x,dplus,plus1 addq.l #1,(SP) gonext * dcode 2+,x,plus1,plus2 addq.l #2,(SP) gonext * dcode 3+,x,plus2,plus3 addq.l #3,(SP) gonext * dcode 4+,x,plus3,plus4 addq.l #4,(SP) gonext * dcode 8+,x,plus4,plus8 addq.l #8,(SP) gonext * dcode 1-,x,plus8,min1 subq.l #1,(SP) gonext * dcode 2-,x,min1,min2 subq.l #2,(SP) gonext * dcode 4-,x,min2,min4 subq.l #4,(SP) gonext * dcode 8-,x,min4,min8 subq.l #8,(SP) gonext * dcode 2*,x,min8,times2 move.l (SP),d0 asl.l #1,d0 move.l d0,(SP) gonext * dcode 4*,x,times2,times4 move.l (SP),d0 asl.l #2,d0 move.l d0,(SP) gonext * dcode 8*,x,times4,times8 move.l (SP),d0 asl.l #3,d0 move.l d0,(SP) gonext * dcode 2/,x,times8,xdiv2 move.l (SP),d0 asr.l #1,d0 move.l d0,(SP) gonext * ; ^elem expects base addr on mstack, and an index on pstack dcode (^ELEM),x,xdiv2,pelem ; return address of array eleme move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.w 0(a3,d7.l),d1 ; fetch width word from header mulu 2(SP),d1 ; multiply index * width add.l d1,d7 ; add to base address addq.l #4,d7 ; skip the header move.l d7,(SP) ; leave on data stack gonext * dcode IDXBASE,x,pelem,idxbas ; idx addr of indexed object move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr addq.l #4,d7 ; skip the idx hdr move.l d7,-(SP) ; leave the ^ixdata gonext * dcode LIMIT,x,idxbas,limit ; limit of indexed object move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.w 2(a3,d7.l),-(SP) ; leave the limit clr.w -(SP) gonext * dcode RANGE?,x,limit,qrange ; index out of range? move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr clr.l d0 move.w 2(a3,d7.l),d0 ; get the limit cmp.l (SP),d0 ; is limit > index? sle d1 ; true if out of range neg.b d1 ; forth boolean move.l d1,-(SP) gonext * dcode AT1,x,qrange,at1 ; at opt for byte elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr add.l (SP)+,d7 ; add the index clr.l d0 move.b 4(a3,d7.l),d0 ; fetch addr+4 (for idx hdr) move.l d0,-(SP) gonext * dcode AT2,x,at1,at2 ; at opt for byte elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.l (SP),d0 ; get the index lsl.w #1,d0 ; index * 2 add.l d0,d7 ; add the index move.w 4(a3,d7.l),d1 ; fetch addr+4 (for idx hdr) ext.l d1 ; sign extend move.l d1,(sp) gonext * dcode AT4,x,at2,at4 ; at opt for long elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.l (SP)+,d0 ; get the index lsl.w #2,d0 ; index * 4 add.l d0,d7 ; add the index move.l 4(a3,d7.l),-(SP) ; fetch addr+4 (for idx hdr) gonext * dcode TO1,x,at4,to1 ; To opt for byte elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr add.l (SP)+,d7 ; add the index move.l (SP)+,d0 move.b d0,4(a3,d7.l) ; store to addr+4 (for idx hdr) gonext * dcode TO2,x,to1,to2 ; To opt for byte elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.l (SP)+,d0 ; get the index lsl.w #1,d0 ; index * 2 add.l d0,d7 ; add the index move.l (sp)+,d1 move.w d1,4(a3,d7.l) ; store to addr+4 (for idx hdr) gonext * dcode TO4,x,to2,to4 ; to opt for long elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.l (SP)+,d0 ; get the index lsl.w #2,d0 ; index * 4 add.l d0,d7 ; add the index move.l (SP)+,4(a3,d7.l) ; store to addr+4 (for idx hdr) gonext * dcode ++4,x,to4,inc4 ; inc opt for long elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.l (SP)+,d0 ; get the index lsl.w #2,d0 ; index * 4 add.l d0,d7 ; add the index move.l (SP)+,d1 ; get increment add.l d1,4(a3,d7.l) ; inc addr+4 (for idx hdr) gonext * dcode ++2,x,inc4,inc2 ; inc opt for word elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.l (SP)+,d0 ; get the index lsl.w #1,d0 ; index * 4 add.l d0,d7 ; add the index move.l (SP)+,d1 ; get increment add.w d1,4(a3,d7.l) ; inc addr+4 (for idx hdr) gonext * dcode ++1,x,inc2,inc1 ; inc opt for byte elements move.l d5,a2 ; pickup base address on mstack move.l (a2),d7 ; base of object in d7 move.l -4(a3,d7.l),d0 ; d0 has ^class of object clr.l d1 move.w 18(a3,d0.l),d1 ; d1 has dlen of object add.l d1,d7 ; d7 points to idx hdr move.l (SP)+,d0 ; get the index add.l d0,d7 ; add the index move.l (SP)+,d1 ; get increment add.b d1,4(a3,d7.l) ; inc addr+4 (for idx hdr) gonext * ; fast left lshift ( val #shift -- val ) dcode <<,x,inc1,shfl popd0 popd1 lsl.l d0,d1 move.l d1,-(SP) gonext * ; fast right lshift ( val #shift -- val ) dcode >>,x,shfl,shfr popd0 popd1 lsr.l d0,d1 move.l d1,-(SP) gonext * dcode (ABS),x,shfr,abs_ ; leave absolute of mstack addr move.l d5,a2 move.l (a2),d0 add.l a3,d0 move.l d0,-(SP) gonext * dcode COUNT,x,abs_,count move.l (SP),d0 add.l #1,(SP) clr.l d1 move.b 0(A3,d0.l),d1 move.l d1,-(SP) gonext * dcode DEPTH,x,count,depth move.l SP,d0 sub.l a3,d0 move.l #(s09-origin),d7 sub.l 0(a3,d7.l),d0 neg.l d0 asr.l #2,d0 pushD0 gonext * dcode FILL,x,depth,fil popD0 fill1 popD1 move.l (SP)+,d7 lea 0(a3,d7.l),a0 fil1 subq.l #1,d1 bmi fil2 move.b d0,(a0)+ bra.s fil1 fil2 gonext * dcode ERASE,x,fil,era clr.l d0 bra.s fill1 * dcode BLANKS,x,era,blanks moveq #$20,d0 bra.s fill1 * dcode +BASE,x,blanks,basadr move.l (SP)+,d7 pea 0(a3,d7.l) ; push absolute address = base+pa gonext * dcode -BASE,x,basadr,minbas move.l a3,d0 sub.l d0,(SP) gonext * dcode ROT,x,minbas,rot popD0 popD1 move.l (SP),d2 move.l d1,(SP) pushD0 move.l d2,-(SP) gonext * dcode PICK,x,rot,pick move.l (SP),d0 asl.l #2,d0 ; index * 4 move.L 0(SP,d0.w),(SP) gonext * dcode RESET,x,pick,rset ; reboot the machine reset * dcode (FDOS),x,rset,fdos ; general file system trap call lea fdtrap(PC),a0 ; stack : (pblock trap --- result) clr.l d1 move.w (SP)+,d1 ; function selector to d0 later move.w (SP)+,(a0) ; move in trap# movea.l (SP)+,a0 ; file control block adda.l a3,a0 ; make it absolute tst.b hwpavail9+3-origin(a3) ; flush cache if necessary beq.s fdt0 moveq #1,d0 _HWPriv fdt0 move.l d1,d0 ; restore d0 fdtrap DC.W 0 ; call Toolbox move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushd0 gonext * dcode (MAKE),x,fdos,make_ move.l (SP)+,a0 ; parm block offset in a0 add.l a3,a0 ; make it absolute _Hcreate ; call Toolbox move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushd0 gonext * dcode (OPEN),x,make_,open_ popd0 ; get access mode in d0 move.l (SP)+,a0 ; parm block offset in a0 add.l a3,a0 ; make it absolute move.b d0,ioPermssn(a0) ; set i/o permission _Hopen ; open the file move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushd0 gonext * dcode (CLOSE),x,open_,close_ move.l (SP)+,a0 ; parm block offset in a0 add.l a3,a0 ; make it absolute _close ; call Toolbox CLOSE move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushd0 gonext * dcode (DELETE),x,close_,delet_ move.l (SP)+,a0 ; parm block offset in a0 add.l a3,a0 ; make it absolute _delete ; call Toolbox DELETE move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushd0 gonext * dcode (READ),x,delet_,read_ popD0 ; pop buffer address into d0 add.l a3,d0 ; make it absolute popD1 ; get count in d1 move.l (SP)+,a0 ; parm block offset in a0 add.l a3,a0 ; make it absolute move.l d0,iobuffer(a0) ; store buffer pointer in parm block move.l d1,ioReqCount(a0) ; store count in parm block _read ; call Toolbox read move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushd0 gonext * dcode (WRITE),x,read_,write_ popD0 ; pop buffer address into d0 add.l a3,d0 ; make it absolute popD1 ; get count in d1 move.l (SP)+,a0 ; parm block offset in a0 add.l a3,a0 ; make it absolute move.l d0,iobuffer(a0) ; store buffer pointer in parm block move.l d1,ioReqCount(a0) ; store count in parm block _write ; call Toolbox read move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushD0 gonext * dcode (LSEEK),x,write_,lseek popD0 ; pickup position offset in D0 popD1 ; pickup positioning mode in D1 move.l (SP)+,a0 ; pop pba add.l a3,a0 move.l d0,ioPosOffset(a0) ; set offset in parm block move.w d1,ioPosMode(a0) ; set mode in parm block _SetFPos move.w ioResult(a0),d0 ; leave result on stack ext.l d0 pushd0 gonext * ; ------- (;CODE) is needed by the following words dcol (;CODE),x,lseek,pscode cfas rfrom,latest,pfa,cfa,store,semis * ; ------- The following words are ;CODE type words dcol CONSTANT,x,pscode,const cfas kreate,comma scode ; points to (;CODE) concode addq.l #4,d6 ; runtime code for constant move.l 0(a3,d6.l),-(SP) gonext * dcol :,I,const,colon ; this colon doesn't set Context cfas qexec,stcsp ; to Current. cfas kreate,rbrak scode colcode suba.l a3,a4 ; convert absolute address to offset move.l a4,-(a6) ; push current IP to Return stack addq.l #4,d6 ; advance WP to pfa of word being def. lea 0(a3,d6.l),a4 ; get absolute addr in A4 gonext * dcol DOES>,x,colon,does cfas rfrom,latest,pfa DATA store-origin scode doescode addq.l #4,d6 suba.l a3,a4 move.l a4,-(a6) move.l 0(a3,d6.l),d7 lea 0(a3,d7.l),a4 addq.l #4,d6 move.l d6,-(SP) gonext * dcol VARIABLE,x,does,varb cfas const scode varcode addq.l #4,d6 move.l d6,-(SP) gonext * dcode OBJMP,x,varb,objmp move.l #(obcode-origin),d0 ; get addr of object code jmp 0(a3,d0.l) ; obj puts its addr on stack * dcol (AB"),x,objmp,abq_ ; abort" runtime word cfas mindup eif. abq11 cfas cr,lit,10+origin,beep,here,count,type cfas lit,63+origin,emit,space,R,count,type,abort else. abq11 cfas rfrom,count,plus,aline,tor ethen. abq11 cfas semis * dcol PREFIX,x,abq_,prefix ; prefix builder for mcfa cfas builds,times4,wcomma,immed cfas does dopref cfas fetpfa cfas cfa,over,wfetch,plus cfas swap_,min4,over,fetch,lit,6+origin,subt cfas fetch,subt,abq_ STR "invalid prefix " cfas state if. pre11 cfas comma,semis then. pre11 cfas exec,semis * ; execute 1cfa of object vector ivar dcode X1CFA,x,prefix,x1cfa move.l d5,a2 ; 1cfa is the fetch/deferred exec routine clr.l d6 move.w (a4)+,d6 ; get offset to ivar add.l (a2),d6 ; add base addr to get 1cfa addr in WP move.l 0(a3,d6.l),d7 ; get code addr in d7 jmp 0(a3,d7.l) * dcol VOCABULARY,x,x1cfa,vocab cfas builds mlit $8120 cfas wcomma,currnt,min2,comma,here,vocl,comma cfas vocl2,does dovocab cfas plus2,contxt2,semis * ; define prefixes for 3cfa variables,vects ddoes PUT,I,vocab,preput,dopref ; 2cfa for all DC.W 8 ddoes PUTDEF,I,preput,prputd,dopref ; 1cfa for sysVe DC.W 4 ; define code handlers for 3cfa variables,vects DATA 0 ; fetch code for sysvect DC.W 8 ; len to vect's pfa from 1cfa dofetchv addq.l #8,d6 ; advance wp to pfa move.l 0(a3,d6.l),-(SP) ; get contents of pfa gonext * DATA preput+4-origin ; store code DC.W 4 ; len to vect's pfa from 1cfa dostore addq.l #4,d6 ; advance wp to pfa move.l (SP)+,0(a3,d6.l) ; get contents of pfa gonext * DATA 0 ; increment code DC.W 8 ; len to vect's pfa from 1cfa doincr addq.l #8,d6 ; advance wp to pfa popd0 add.l d0,0(a3,d6.l) ; increment contents of pfa gonext * DC.W 12 doexec add.l #12,d6 move.l 0(a3,d6.l),d6 ; get address to execute move.l 0(a3,d6.l),d7 ; get contents of CFA jmp 0(a3,d7.l) ; execute the code DC.W 12 ; execute a system vector table entry dosexec add.l #12,d6 move.l userdp(PC),d0 ; rel base of system vector table add.l 0(a3,d6.l),d0 ; add offset into table move.l 0(a3,d0.l),d1 ; get vector contents beq dodeflt ; if 0, exec default move.l d1,d6 bra.s sexec dodeflt move.l 4(a3,d6.l),d6 ; get default cfa to execute sexec move.l 0(a3,d6.l),d7 ; get contents of CFA jmp 0(a3,d7.l) ; execute the code * DATA prputd+4-origin DC.W 8 ; set offset, default for system vector doputdef addq.l #8,d6 move.l (SP)+,0(a3,d6.l) ; set the offset move.l (SP)+,4(a3,d6.l) ; set the default gonext * DATA preput+4-origin DC.W 4 ; set sys vector table entry for this vect doputsv addq.l #4,d6 move.l userdp(PC),d0 add.l 0(a3,d6.l),d0 ; add the offset move.l (SP)+,0(a3,d0.l) ; store the vector gonext * DC.W 12 ; len to value's pfa from 1cfa dofetch add.l #12,d6 ; advance wp to pfa move.l 0(a3,d6.l),-(SP) ; get contents of pfa gonext * dcol ",",x,prputd,comma ; begin comman dict entry cfas here,store,pfour,allot,semis * dcol "W,",x,comma,wcomma ; begin Wcomma dict entry cfas here,wstore,lit,2+origin,allot,semis * dcol "C,",x,wcomma,ccomma ; begin C, dict entry cfas here,cstore,pone,allot,semis * dcol @PFA,x,ccomma,fetpfa cfas mfind,zequ,abq_ STR "not found " cfas drop,semis * dcol LFA,x,fetpfa,lfa mlit 8 cfas subt,semis * dcol NFA,x,lfa,nfa mlit 9 cfas subt mlit -1 cfas traver,semis * dcol PFA,x,nfa,pfa mlit 1 cfas traver,lit,9+origin,plus,semis * dcol >LINE,x,pfa,toline cfas docs if. L100 cfas min2 then. L100 cfas semis * dcol LINE>,x,toline,linefm cfas docs if. L101 cfas plus2 then. L101 cfas semis * dcol ALIGN,x,linefm,aline cfas dup mlit 1 cfas and_,plus,semis * dcol DECIMAL,x,aline,decim mlit $0a cfas base2,semis * dcol HEX,x,decim,hex mlit $10 cfas base2,semis * dcol (."),x,hex,dotq_ cfas r,count,dup,plus1,aline,rfrom,plus,toR,type cfas semis * dcol PAD,x,dotq_,pad mlit padbuf-origin cfas semis * dcol #>,x,pad,enum cfas drop2,hld,pad,over,subt,semis * dcol HOLD,x,enum,hold DATA pmone-origin cfas hld1,hld,cstore,semis * dcol SIGN,x,hold,sign cfas rot,zless if. Z3 mlit $2d cfas hold then. Z3 cfas semis * dcol #,x,sign,sharp cfas base,msmod,rot mlit 9 cfas over,less if. Z4 mlit 7 cfas plus then. Z4 mlit $30 cfas plus,hold,semis * dcol #S,x,sharp,sharps begin. Z5 cfas sharp,dup2,or_,zequ until. Z5 cfas semis * dcol <#,x,sharps,snum cfas pad,hld2,semis * dcol D.R,x,snum,ddotr cfas toR,swap_,over,dabs,snum,sharps,sign,enum,rfrom cfas over,subt,spaces,type,semis * dcol D.,x,ddotr,ddot mlit 0 cfas ddotr,space,semis * dcol .,x,ddot,dot cfas sToD,ddot,semis * dcol U.,x,dot,udot mlit 0 cfas ddot,semis * dcol .R,x,udot,dotR cfas toR,sToD,rfrom,ddotr,semis * dcol ?,x,dotR,quest cfas fetch,dot,semis * dcol SPACE,x,quest,space cfas bl,emit,semis * dcol SPACES,x,space,spaces mlit 0 do. Z7 cfas bl,emit loop. Z7 cfas semis * dcol -TRAILING,x,spaces,mtrail cfas dup mlit 0 do. Z8 cfas over,over,plus,min1,cfetch,bl,subt eif. Z10 cfas leave else. Z10 cfas min1 ethen. Z10 loop. Z8 cfas semis * dcol N>COUNT,x,mtrail,ncount cfas count mlit $1f cfas and_,semis * dcol ID.,x,ncount,iddot cfas ncount,type,space,semis * dcol EMIT,x,iddot,emit cfas dup,emitvec,pemitv,pone ; send the char via Quickdraw cfas out1,semis * dcol TYPE,x,emit,type cfas dup,out1,dup2,typevec,ptypev,semis dcol CR,x,type,cr cfas crvec,pcrvec,semis * dcol CONTBOT,x,cr,contbot cfas port_,lit,windowsize+origin,plus,plus4 cfas wfetch,semis * dcol CONTTOP,x,contbot,conttop cfas port_,lit,windowsize+origin,plus cfas wfetch,semis * dcol ?LEAD,x,conttop,qlead ; return proper leading for fo cfas port_,lit,txsize+origin,plus,wfetch cfas lit,120+origin,star,lit,50+origin,plus ; Increase 120 f cfas lit,100+origin,slash,semis * dcol ?LINES,x,qlead,qlines ; number of even lines in port cfas qlead,contbot,conttop ; bottom-top of content rgn cfas subt,lit,5+origin,subt, ; less first line location cfas over,plus1,subt ; minus ?LEAD+1 cfas swap_,slash,semis ; divided by ?LEAD * dcol BOTTOM,x,qlines,scrbot ; coordinate of screen bottom cfas conttop,plus4,qlead,qlines,star,plus cfas semis * dcol (CR),x,scrbot,cr_ ; simulate a CR in Quickdraw cfas dotcur,fetxy,swap_,drop,lit,8+origin,swap_ cfas dup,scrbot,grt eif. x27 cfas pzer,qlead,minus,scroll,gotoxy else. x27 cfas qlead,plus cfas gotoxy ethen. x27 cfas dotcur,semis * dcol (BS),x,cr_,bs_ cfas dotcur,fetxy,swap_,lit,6+origin,subt,lit,8+origin,max cfas swap_,dup2,gotoxy,curs_,pzer,curs_2 cfas bl,emit,curs_2,gotoxy,dotcur,semis * dcol ?TERMINAL,x,bs_,qterm cfas lit,$28+origin,qevt,semis * dcol (KEY),x,qterm,key_ mlit $2A ; kbd and mouse events cfas getevt,lit,2+origin,grt eif. Z100 cfas ftemsg,lit,$00ff+origin,and_ else. Z100 cfas pmone ethen. Z100 cfas semis * dcol (DKEY),x,key_,dkey_ cfas ufcb,pone,lit,ftwork ; read 1 char from disk cfas read_,dup,dkerr2 eif. y10 cfas keystor,pone,curs_2 ; restore to terminal if err cfas lit,13+origin else. y10 cfas lit,ftwork,cfetch ; leav char on stack ethen. y10 cfas qpause,semis * dcol KEY!,x,dkey_,keystor ; reset KEY to keyboard cfas lit,key_,keyvec2,semis * dcol KEY,x,keystor,key cfas keyvec,semis ; vectored key * dcol <",x,key,diskin ; set to disk key inpu cfas ufcb,close_,dot ; close the oldfile cfas lit,useFcb,lit,80+origin,era,pzer,curs_2 cfas lit,34+origin,word,here,dup,cfetch,plus1 cfas lit,useFname,swap_,cmove cfas lit,useFname,basadr,lit,useFcb,sflptr cfas ufcb,pone,open_,dot cfas cr,lit,dkey_,keyvec2,semis * ; ------------ Disk words for FORTH screen handling dcol !FPTR,x,diskin,sflptr ; ( ^fname pblock -- ) cfas lit,18+origin,plus,store,semis * dcol ?COMP,x,sflptr,qcomp cfas state,zequ,abq_ STR "compilation only " cfas semis * dcol ?DP,x,qcomp,qdp ; dp grown into heap? cfas room,pone,less,abq_ STR " out of room " cfas semis * dcol ?STACK,x,qdp,qstack cfas spfet,s0,swap_,uless cfas abq_ STR "empty stack " cfas semis * dcol ?EXEC,x,qstack,qexec cfas state,cstate,or_,abq_ ; err if class or forth compile STR "run state only " cfas semis * dcol ?PAIRS,x,qexec,qpairs cfas subt,abq_ STR "unpaired conditionals " cfas semis * dcol ?CSP,x,qpairs,qcsp cfas spfet,csp,subt,abq_ STR "definition not finished " cfas semis * dcol (NUMBER),x,qcsp,num_ begin. Z27 cfas plus1,dup,tor,cfetch,base,digit while. Z27 cfas swap_,base,ustar,drop,rot,base cfas ustar,dplus,dpl,plus1 if. Z28 cfas pone,dpl1 then. Z28 cfas rfrom repeat. Z27 cfas rfrom,semis * dcol ?NUM,x,num_,qnum ; ( addr -- d t OR f ) cfas pzer,pzer,rot,dup,plus1,cfetch mlit $2d cfas equals,dup,tor,plus,pmone begin. Z30 cfas dpl2,num_,dup,cfetch,bl,subt while. Z30 cfas dup,cfetch,lit,$2e+origin,subt if. zz177 cfas rfrom,drop2,drop2,pzer,semis then. zz177 cfas pzer repeat. Z30 cfas drop,rfrom if. Z31 cfas dminus then. Z31 cfas pone,semis * dcol NUMBER,x,qnum,number ; ( addr -- d ) cfas qnum,zequ,abq_ STR "not found " cfas semis * dcol LITERAL,I,number,liter cfas state if. Z32 cfas dup,lit DATA $10000 cfas less,over,zless,zequ,and_ eif. zz39 cfas comp,wlit,wcomma else. zz39 cfas comp,lit,comma ; builds word lit if n>=0 and n<$10000 ethen. zz39 then. Z32 cfas semis * dcol EXPECT,x,liter,expect cfas over,plus,over do. Z33 cfas key,dup,lit,8+origin,equals ; bs ? eif. Z34 cfas drop,dup,i,equals,dup,rfrom,min2,plus,tor eif. Z35 cfas lit,10+origin,beep else. Z35 cfas bs_ ethen. Z35 cfas pzer else. Z34 cfas dup,zequ if. y118 cfas drop,lit,32+origin ; map null to space then. y118 cfas dup,lit,$0d+origin,equals eif. Z36 cfas leave,drop,pzer,pzer,cr else. Z36 cfas dup ethen. Z36 cfas r,cstore,pzer,r,plus1,cstore ethen. Z34 cfas echovec loop. Z33 cfas drop,semis * dcol WORD,x,expect,word cfas tib cfas in,plus,swap_,enclos cfas word_,semis * dcol WORD",x,word,wordq ; lower-case version of word cfas tib,in,plus,lit,34+origin,enclos cfas lcword,here,semis * dcol FIND,x,wordq,mfind cfas bl,word,ufind,dup,zequ if. w72 cfas drop,here,contxt,fetch cfas find_,dup,zequ if. Z38 cfas contxt,currnt,subt if. Z40 cfas drop,here,latest,find_ then. Z40 then. Z38 then. w72 cfas semis * ADJST ; X - null word lkx DC.B $C1 DC.B $00 DATA lkmfind-origin DATA colcode-origin ; not Fig standard - cfas rfrom,drop ; note: doesn't support Forth screens cfas semis * dcol "S,",x,x,scomma ; begin S, dict entry cfas here,dup,cfetch,plus1,dup cfas allot,pone,and_ if. sc10 cfas pzer,ccomma then. sc10 cfas dup,rot,toggle,semis * dcol (CREATE),x,scomma,creat_ cfas here,pone,and_ if. Z430 cfas pzer,ccomma then. Z430 cfas docs if. Z410 cfas line_,wcomma then. Z410 cfas mfind if. Z420 cfas drop,nfa,iddot,dotq_ STR "is redefined " cfas cr then. Z420 cfas lit,$80+origin,scomma cfas latest,comma,currnt cfas store,here,plus4,comma,semis * dcol (INTRP),x,creat_,intrp_ begin. Z43 cfas mfind eif. Z44 cfas state,less eif. Z45 cfas cfa,comma else. Z45 cfas cfa,exec ethen. Z45 else. Z44 cfas here,number,dpl,plus1 eif. Z46 cfas dliter else. Z46 cfas drop,liter ethen. Z46 ethen. Z44 cfas qdp,qstack again. Z43 cfas semis * dcol !CSP,x,intrp_,stcsp cfas spfet,csp2,semis * dcol QUERY,x,stcsp,query cfas tib,lit,$99+origin cfas expvec,pzer,in2,semis * dcol <[,I,query,lbrak mlit 0 cfas state2,semis * dcol ]>,x,lbrak,rbrak mlit $c0 cfas state2,semis * dcol DEFINITIONS,x,rbrak,defs cfas contxt,currnt2,semis * dcol